TableStoreLines Subroutine

private subroutine TableStoreLines(unit, lines)

read the lines of a table which are stored in an array of strings. Non significative lines (i.e. comments or blank lines) are ignored. Subroutine supposes that the cursor is sync to the first line after the keyword 'Table Start'. hence it is must benn called after a call to tableFileSync. Arguments: unit file in which table is contained lines returned collection of linestable

Arguments

Type IntentOptional Attributes Name
integer(kind=short), intent(in) :: unit
character(len=LINELENGTH), intent(out), POINTER :: lines(:)

Variables

Type Visibility Attributes Name Initial
integer(kind=long), public :: count
type(LinkedList), public, POINTER :: current
integer(kind=long), public :: i
integer(kind=short), public :: ios
type(LinkedList), public, POINTER :: list
type(LinkedList), public, POINTER :: next
type(LinkedList), public, POINTER :: previous
character(len=LINELENGTH), public :: string

Derived Types

type ::  ..\..\LinkedList

Components

Type Visibility Attributes Name Initial
character(len=LINELENGTH), public :: line
type(LinkedList), public, POINTER :: next

Source Code

SUBROUTINE TableStoreLines &
  ( unit, lines )

! Module used:
USE StringManipulation, ONLY: &
! imported routines:
StringCompact, StringToUpper, &
StringSplit

IMPLICIT NONE

! Subroutine arguments
! Scalar arguments with intent(in):
INTEGER (KIND = short), INTENT (IN) :: unit

! Array arguments with intent (out):
CHARACTER (LEN = LINELENGTH), INTENT (OUT), POINTER :: lines (:)
! Local scalars:
INTEGER (KIND = short) :: ios
CHARACTER (LEN = LINELENGTH)  :: string
INTEGER (KIND = long)  :: count
INTEGER (KIND = long)  :: i

! Local Type definition:
!define a dynamic list of strings
TYPE LinkedList
    TYPE(LinkedList), POINTER :: next
    CHARACTER (LEN = LINELENGTH) :: line
END TYPE LinkedList

! Local Arrays:
TYPE (LinkedList), POINTER :: list
TYPE (LinkedList), POINTER :: current
TYPE (LinkedList), POINTER :: next
TYPE (LinkedList), POINTER :: previous

!------------end of declaration------------------------------------------------

!initialization    
string = ''
count = 0
NULLIFY (list)
! scan file till end of the table keyword TABLE END
DO WHILE ( .NOT. StringCompact (StringToUpper (string) ) == "TABLE END" )
  READ (unit, "(a)",IOSTAT = ios) string
  IF ( ios > 0 ) THEN !reached the end of file without finding table end
    !CALL Catch
  END IF
  
  string = StringCompact (string)
  IF ( string == '' .OR. string(1:1) == "#" ) THEN !skip element
  ELSE !found new element 
      !increment counter
      count = count + 1
      !add an element to list
      IF(.NOT.ASSOCIATED(list)) THEN
           ALLOCATE(list)     !riconosco il primo elemento da inserire
           current => list
       ELSE
           ALLOCATE(current%next)
           current => current%next
       END IF
       !store line in the list.
       current % line = string
  END IF
END DO

!allocate space for significant lines
ALLOCATE ( lines (count) )
!transfer lines from temporary list to tab
current => list ! current is an alias of list
DO i = 1, count
  lines (i) = current % line
  previous => current
  current => current % next !current is an alias of next element of the list
  DEALLOCATE(previous)    !free memory of the previous element 
END DO

END SUBROUTINE TableStoreLines